TimeIndex Function

private function TimeIndex(ncId, refTime, timeUnit, time) result(index)

Calculate the index to extract the corresponding slice from netcdf file.

Arguments

Type IntentOptional Attributes Name
integer(kind=short), intent(in) :: ncId

NetCdf Id for the file

type(DateTime), intent(in) :: refTime

reference time to calculate time index

character(len=*) :: timeUnit
type(DateTime), intent(in) :: time

time to calculate index from reference time

Return Value integer(kind=short)


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: CurrentTimeNumber
character(len=80), public :: attribute
integer, public :: current
integer(kind=long), public :: difference
integer, public, DIMENSION(NF90_MAX_VAR_DIMS) :: dimIDs
logical, public :: found
integer(kind=short), public :: i

loop index

integer(kind=short), public :: idTime

Id of the variable containing information on time ccordinate

integer(kind=short), public :: length

length of time dimension

integer(kind=short), public :: nAtts

number of global attributes

integer(kind=short), public :: nDims

number of dimensions

integer(kind=short), public :: nVars

number of variables

integer(kind=short), public :: ncStatus

error code return by NetCDF routines

integer, public :: slice(2)
character(len=19), public :: str
character(len=25), public :: string
integer(kind=short), public :: timeNumber
character(len=100), public :: variableName

Source Code

FUNCTION TimeIndex &
!
(ncId, refTime, timeUnit, time) &
RESULT (index)

USE Units, ONLY: &
! Imported parameters:
minute, hour, day, month

USE StringManipulation, ONLY: &
!Imported routines:
StringtOsHORT

IMPLICIT NONE

! Arguments with intent(in):
INTEGER (KIND = short), INTENT(IN)   :: ncId  !!NetCdf Id for the file
TYPE (DateTime), INTENT(IN)  :: refTime  !!reference time to calculate time index
CHARACTER (LEN = *) :: timeUnit
TYPE (DateTime), INTENT (IN)  :: time !!time to calculate index from reference time

! Local variables:
INTEGER (KIND = short) :: index
INTEGER (KIND = long)  :: difference
INTEGER (KIND = short) :: ncStatus !!error code return by NetCDF routines
INTEGER (KIND = short) :: nDims !!number of dimensions
INTEGER (KIND = short) :: nVars !!number of variables
INTEGER (KIND = short) :: nAtts !!number of global attributes
INTEGER (KIND = short) :: length !!length of time dimension
INTEGER (KIND = short) :: idTime !!Id of the variable containing 
                                 !!information on time ccordinate   
INTEGER (KIND = short) :: timeNumber   
INTEGER (KIND = short) :: CurrentTimeNumber     
CHARACTER (LEN = 80)   :: attribute
CHARACTER (LEN = 100)  :: variableName
INTEGER (KIND = short) :: i !!loop index
INTEGER                :: slice (2)
INTEGER                :: current
LOGICAL                :: found
CHARACTER (LEN = 25)   :: string
CHARACTER (LEN = 19)   :: str
INTEGER, DIMENSION(NF90_MAX_VAR_DIMS) :: dimIDs
!------------end of declaration------------------------------------------------

!inquire dataset to retrieve number of dimensions, variables 
!and global attributes
ncStatus = nf90_inquire(ncId, nDimensions = nDims, &
                        nVariables = nVars,        &
                        nAttributes = nAtts        )
                  
CALL ncErrorHandler (ncStatus)

!search for time variable
DO i = 1, nVars
  attribute = ''
  ncStatus = nf90_get_att (ncId, varid = i, name = 'standard_name', &
                           values = attribute)
  
  IF (ncStatus == nf90_noerr) THEN 
    IF ( attribute(1:4) == 'time' ) THEN
      idTime = i 
      EXIT   
    END IF
  ELSE !standard_name is not defined: search for variable named 'time'
     !ncStatus = nf90_inq_varid (ncId, 'time', varid = i )
     ncstatus = nf90_inquire_variable(ncId, varId = i, name = variableName)
     IF (LEN_TRIM(variableName) == 4 .AND. &
         variableName(1:4) == 'time' .OR. &
         LEN_TRIM(variableName) == 4 .AND. &
         variableName(1:4) == 'Time' .OR. &
         LEN_TRIM(variableName) == 5 .AND. &
         variableName(1:5) == 'Times' ) THEN !variable 'time' found
       idTime = i 
       EXIT 
     END IF
  END IF
END DO

!retrieve time length
length = GetTimeSteps (ncId) 
!ncStatus = nf90_inquire_variable(ncid, idTime, dimids = dimIDs)
!CALL ncErrorHandler (ncStatus)
!
!ncStatus = nf90_inquire_dimension (ncId, dimid = dimIDs(2), len = length)
!CALL ncErrorHandler (ncStatus)

!search for current time
found = .FALSE.
IF (DateTimeIsDefault(refTime)) THEN
  !build datetime string as used in netcdf file i.e 2007-10-11_00:00:00
  timeString = time
  !2000-01-01T00:00:00+00:00
  timeString = timeString(1:10) // '_' // timeString(12:19)
   !CurrentTimeNumber  = StringToShort (timeString)      
  DO i = 1, length
     slice(1) = 1
     slice(2) = i
     ncStatus = nf90_get_var (ncId, idTime, str , start = slice)
     CALL ncErrorHandler (ncStatus)
     IF (TRIM(str) == TRIM(timeString)) THEN
       found = .TRUE.
       index = i
       EXIT
     END IF
    END DO
ELSE
    !calculate time span in appropriate unit
    difference = time - refTime
    SELECT CASE (timeUnit)
      CASE ('minutes')
        difference = difference / INT(minute)
      CASE ('hours')
        difference = difference / INT(hour)
      CASE ('days')
        difference = difference / INT(day)
      CASE ('months')
        difference = difference / INT(month)
    END SELECT  

    DO i = 1, length
     slice(1) = i
     ncStatus = nf90_get_var (ncId, idTime, current , start = slice)
     CALL ncErrorHandler (ncStatus)
     IF (current == difference) THEN
       found = .TRUE.
       index = i
       EXIT
     END IF
    END DO
END IF

IF ( .NOT. found ) THEN
  string = time
  CALL Catch ('error', 'GridLib',        &
    'time not found in netcdf file: ',  &
    argument = string )
END IF

END FUNCTION TimeIndex